home *** CD-ROM | disk | FTP | other *** search
/ Language/OS - Multiplatform Resource Library / LANGUAGE OS.iso / prolog / modprolg / mod-prol.lha / Prolog / Examples / search.pl < prev    next >
Text File  |  1992-05-26  |  1KB  |  42 lines

  1.         solvedfs(Node,Solution) :- 
  2.             df([],Node,Solution).
  3.  
  4.         df(Path,Node,[Node|Path]) :- 
  5.             goal(Node).
  6.         df(Path,Node,Sol) :- 
  7.             s(Node,Node1),
  8.             not member(Node1,Path), % No Cycles!
  9.             df([Node|Path],Node1,Sol).
  10.  
  11.         solvedfs(Node,Solution) :- 
  12.             bf([[Node]],Solution).
  13.  
  14.         bf([[Node|Path]|_],[Node|Path]) :-
  15.             goal(Node).
  16.         bf([[N|Path]|Paths],Solution) :-
  17.             bagof([M,N|Path],
  18.                   (s(N,M),not member(M,[N|Path])),
  19.                   Newpaths), % Newpaths = acyclic extensions of [N|Path]
  20.             append(Paths,Newpaths,Paths1), !,
  21.             bf(Paths1,Solution);
  22.             bf(Paths,Solution).   % Case that N has no successors.
  23.  
  24.         goal([_,_,_,_,_,_,_,_]).
  25.  
  26.         s(Queens,[Queen|Queens]) :-
  27.             member(Queen,[1,2,3,4,5,6,7,8]),
  28.         not member(Queen, Queens),
  29.             safe([Queen|Queens]).
  30.  
  31.         safe([]).
  32.         safe([Queen|Others]) :-
  33.             safe(Others),
  34.             noattack(Queen,Others,1).
  35.  
  36.         noattack(_,[],_).
  37.         noattack(Y,[Y1|Ylist],Xdist) :- 
  38.             Y1 - Y =\= Xdist,
  39.             Y - Y1 =\= Xdist, 
  40.             Dist1 is Xdist + 1,
  41.             noattack(Y, Ylist, Dist1).
  42.